home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
SGI Varsity Update 1998 August
/
SGI Varsity Update 1998 August.iso
/
docs6.5
/
relnotes
/
ftn77_fe
/
ch6.z
/
ch6
Wrap
Text File
|
1998-07-29
|
14KB
|
462 lines
- 1 -
7.2.1 Fortran 77 Front-End Release Notes
- 2 -
DDDDooooccccuuuummmmeeeennnntttt NNNNuuuummmmbbbbeeeerrrr 000000007777----1111666655559999----000011110000
6. _B_u_g__F_i_x_e_s
This chapter briefly describes the bugs that
have been fixed in the compiler since release
7.1. Some of the headings are followed by a
Silicon Graphics incident report number.
6.1 _B_u_g__F_i_x_e_s__I_n__M_I_P_S_p_r_o__7_._2_._1
+o Fortran datapools cause core dump on O2
machines with the R5000.
An application would run correctly on O2
machines with the R10000, but fail on O2's
running with R5000's. The symptom would
appear as:
$ ./testdp
map_datapool: trouble sharing /usr/tmp/DP_hello at address 5FDB2000
map_datapool (mmap): Invalid argument
Abort (core dumped)
The mmap system call has some restrictions
which were not being satisfied by the
datapool implementation. The workaround was
to allow the user to specify a datapool pad
size through a new command line option
-FE:datapool_pad. When this option is used
a new entry point in the library is called
to mmap the datapool. The runtimes from
patch 2759 are required for this workaround
(Bug #517508).
+o Intrinsic len broken when -i2 -n32 used
With the 7.2 compilers, compiling this code
with -i2 -n32 gives declaration conflicts
on intrinsic LEN function.
- 3 -
%cat foo.f
INTEGER*2 LEN
INTRINSIC LEN
CALL SUB(LEN('ABC'))
END
SUBROUTINE SUB(I)
INTEGER*2 I
PRINT *,I
END
%f77 -i2 -n32 foo.f
"foo.f", line 2: error(2085): declaration conflicts with previous
specifications
INTRINSIC LEN
^
1 error detected in the compilation of "foo.f".
This has been fixed (Bug #527165).
+o -i2 broken with -n32 or -64
Compiling the following program with -i2
under -n32 or -64 would result in an error:
$ cat tst.f
REAL*4 A(96000)
REAL*4 B(32000)
EQUIVALENCE (B,A(64001))
PRINT *,A(1),B(1)
END
$ f77 -i2 -n32 tst.f
"tst.f", line 3: warning(2057): integer conversion resulted in
truncation
EQUIVALENCE (B,A(64001))
"tst.f", line 3: error(2134): subscript out of range
EQUIVALENCE (B,A(64001))
This has been fixed (Bug #559245).
+o Compilation failures when using -craylibs.
The following program would cause a compile
time abort when using the -craylibs option:
- 4 -
%cat readkk.f
SUBROUTINE READKK(A,NDIME,NU) READKK 2
IMPLICIT REAL*8(A-H,O-Z) READKK 3
DIMENSION A(NDIME,NDIME) READKK 4
READ (NU) A READKK 5
RETURN READKK 6
END READKK 7
%f77 -c -O3 -craylibs readkk.f
Signal: Segmentation fault in Global Optimization -- Mainopt Lowering phase.
Error: Signal Segmentation fault in phase Global Optimization -- Mainopt
Lowering -- processing aborted
This has been fixed (Bug #576655, #538635)
+o Bus Error when compiling with -IPA
Compiling a program that contains an
initialization of an element of a COMMON
block would abort with a bus error in the
compiler if the program linked with a
shared object that contains a declaration
of the same COMMON block and the
compilation was done with the ----IIIIPPPPAAAA option.
This has been fixed (Bug #521139).
+o Limit on number of files which could be
compiled from one f77 command line when
floating licenses were used
The Fortran 77 compiler would stop and
issue the following warnings when trying to
compile more files than the open file
descriptor limit on a single command line
under floating licensing.
For Example:
(Floating Licenses being used)
%limit descriptors
descriptors 200
%f77 *.f (more than 200 .f files in current directory)
file196.f:
cc: Error: can't create output file: /tmp/ctmpa001YG
: Too many open files
This has been fixed (Bug #556876).
- 5 -
6.2 _B_u_g__F_i_x_e_s__I_n__M_I_P_S_p_r_o__7_._2
+o Very slow compilation of Fortran file.
Under certain circumstances, the
compilation of a certain Fortran source
code file would take approximately 45
minutes to compile.
This has been fixed (Bug #475298).
+o Datapool: padding between datapool elements
Datapool items were always aligned on
doubleword boundary, regardless of their
types. This has been fixed so that they
are aligned according to the type of each
item. (Bug #453040).
+o Compiler coredumps when compiling with -32
-g option.
Under certain circumstances, the compiler
would dump core when compiling files -32
-g. This has been fixed. (Bug #372302)
+o Namelist I/O problem
Fixed the problem in namelist I/O which
resulted in the error "variable not in
namelist" (Bug #359690)
+o Structures misalignemnt
Fixed a problem where structures were not
aligned properly and caused a bus error.
(Bug #443526)
+o Rejecting -p flag
The following code would core dump when
compiled with -p.
a = 1.0
b = 2.0
c = matmul(a,b)
print *, c
stop
end
As -p is no longer supported; the user
should use ssrun -pcsamp, etc. to do pc-
sampling. The compiler was changed to
reject -p with a warning. (Bug #444089)
+o f77 -n32 causes problems reading
unformatted files
Under certain circumstances programs
- 6 -
compiled -n32 would have problems reading
unformatted files. This has been fixed.
(Bug #454102)
+o n32/64 f77 compilers do not accept
-NCxxxx, xxxx>1000
Code with more than 1000 continuation lines
would get an error similar to the
following:
Command-line error(2414): Invalid number of continuation lines in -NC
This has been fixed. (Bug #461738)
+o f77 structure alignment problem when using
-32 compiler option, bus error
This has been fixed. (Bug #468837)
+o f77 unformatted write with negative implied
do fails
The following code fragment would not be
compiled correctly:
c
c This does not work when using f77 -mips4
c
open(11,file='file1.dat',form='unformatted')
write(11) imax,1,1
write(11) (xt(i),i=imax,1,-1),
& (yt(i),i=imax,1,-1),
& (zt(i),i=imax,1,-1)
close(11)
c
This has been fixed. (Bug #468899)
+o f77: compiler error: can't find local for
idn = 10, offset = 40
The following code would not be compiled
correctly -static -g -c:
SUBROUTINE MAPCRV (XMAP, NPARRA, DATSTR, ERR)
CHARACTER DATSTR*(*)
GO TO 10
ENTRY MAPSYM (XMAP, NPARRA, ISYM, KOLREF, HTSYM, SYMANG, XLTABL, N
+ LTABL, DATSTR, ERR)
10 CONTINUE
RETURN
END
- 7 -
This has been fixed. (Bug #469034)
+o Assertion failure with -r8 -O3 during LNO
phase
Under certain circumstances, an f77
compilation would abort with the following
error message:
### Assertion failure at line 270 of ../../be/lno/snl_trans.cxx:
### Compiler Error in file foo1.f during Loop Nest Optimizer phase:
### Projection failed!
f77 INTERNAL ERROR: /usr/lib32/cmplrs/be returned non-zero status 1
This has been fixed. (Bug #473750).
+o f77 -64 fails on close of non-existent file
Closing a non-existent file causes error
when the executable was compiled with the
"-64" option. This has been fixed. (Bug
#477232)
+o mfef77 core dumps with undefined variable
When compiling incorrect code with -n32
option, in which an array has no type
declaration, /usr/lib32/cmplrs/mfef77 would
core dump. This has been fixed. (Bug
#492186)
+o Optimization -O3 gives wrong result in f77
version 7.1
Under a certain condition using -O3 in
conjunction with f77 -n32 would produce a
program which gives incorrect results.
This has been fixed. (Bug #517093)